home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Language/OS - Multiplatform Resource Library
/
LANGUAGE OS.iso
/
prolog
/
brklyprl.lha
/
Comp
/
objcode.pl
< prev
next >
Wrap
Text File
|
1989-04-14
|
2KB
|
43 lines
/* Copyright (C) 1988, 1989 Herve' Touati, Aquarius Project, UC Berkeley */
/* Copyright Herve' Touati, Aquarius Project, UC Berkeley */
% Turn partial object code, which still contains the
% hierarchy of goals and disjunctions, into a uniform list.
% The control instructions for disjunctions are compiled and
% the labels for the cut instructions are instantiated.
objcode(PartObj, ObjCode) :-
xobjcode(PartObj, ObjCode-[], proc, _), !.
xobjcode([], Link-Link, _, _).
xobjcode([cutd|RestCode], [cutd(CutLbl)|C]-Link, CutLbl, yes) :-
xobjcode(RestCode, C-Link, CutLbl, _).
xobjcode([Code-L|RestCode], Code-Link, CutLbl, IsCut) :-
xobjcode(RestCode, L-Link, CutLbl, IsCut).
xobjcode([(X;Choices)|RestCode],
[begin(disj),try(else,L1)|ChCode]-Link, CutLbl, IsCut) :-
xobjcode(X, ChCode-ChLink, L1, _),
ChLink=[execute(EndLbl),label(L1)|C3],
xdiscode(Choices, C3-L, EndLbl),
L = [end(disj)|NewL],
xobjcode(RestCode, NewL-Link, CutLbl, IsCut).
xdiscode((X;Choices), [retry(else,L2)|ChCode]-Link, EndLbl) :-
xobjcode(X, ChCode-ChLink, L2, _),
ChLink=[execute(EndLbl),label(L2)|C3],
xdiscode(Choices, C3-Link, EndLbl).
xdiscode(LastChoice, Code-Link, EndLbl) :-
xobjcode(LastChoice, ChCode-ChLink, CutLbl, IsCut),
lastchoice(IsCut,CutLbl,EndLbl,Code,ChCode,ChLink,L),
L=[label(EndLbl)|Link].
% Handle case of cut in last choice:
lastchoice(IsCut,CutLbl,EndLbl,Code,ChCode,ChLink,L) :-
IsCut==yes, !,
Code=[retry(else,CutLbl)|ChCode],
ChLink=[execute(EndLbl),label(CutLbl),trust(else,fail),fail/0|L].
lastchoice(IsCut,CutLbl,EndLbl,Code,ChCode,ChLink,L) :-
Code=[trust(else,fail)|ChCode],
ChLink=L.